home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / prlg_ndc.z / prlg_ndc
Text File  |  1993-08-16  |  4KB  |  197 lines

  1.  
  2. This file contains Prolog and C source code for several benchmarks comparing
  3. the execution speed of Aquarius Prolog and the MIPS C compiler, both running
  4. on a MIPS processor.
  5.  
  6. Execution speed results (June 12, 1990):
  7.  
  8. Benchmark    Prolog      C (no opt.)    C (best opt.)
  9.  
  10. tak(24,16,8)    1.2        2.1        1.6
  11. fib(30)        1.5        2.0        1.6
  12. han(20,1,2,3)    1.3        1.6        1.5
  13. quicksort    2.8        3.3        1.4
  14.  
  15. All timings are in user seconds (with 'time') measured on the same 25 MHz MIPS
  16. processor.  The Prolog versions are compiled with the Aquarius Prolog compiler
  17. under development at Berkeley.  The C versions are compiled with the MIPS C
  18. compiler, with no optimization and best optimization (usually level 4).
  19.  
  20. Disclaimer: these benchmarks have particularly easy translations to C.  This
  21. comparison is intended only to dispel the notion that a logic language such as
  22. Prolog is inherently slow due to its expressive power.  The results do not
  23. necessarily hold for other programs.
  24.  
  25.     Peter Van Roy
  26.     vanroy@ernie.berkeley.edu
  27.  
  28. -------------------------------------------------------------------------------
  29.  
  30. /* C version of tak benchmark */
  31.  
  32. #include <stdio.h>
  33.  
  34. int tak(x,y,z)
  35. int x, y, z;
  36. {
  37.   int a1, a2, a3;
  38.   if (x <= y) return z;
  39.   a1 = tak(x-1,y,z);
  40.   a2 = tak(y-1,z,x);
  41.   a3 = tak(z-1,x,y);
  42.   return tak(a1,a2,a3);
  43. }
  44.  
  45. main()
  46. {
  47.   printf("%d\n", tak(24, 16, 8));
  48. }
  49.  
  50. -------------------------------------------------------------------------------
  51.  
  52. /* Prolog version of tak benchmark */
  53.  
  54. main :- tak(24,16,8,X), write(X), nl.
  55.  
  56. tak(X,Y,Z,A) :- X =< Y, Z = A.
  57. tak(X,Y,Z,A) :- X > Y,
  58.         X1 is X - 1, tak(X1,Y,Z,A1),
  59.         Y1 is Y - 1, tak(Y1,Z,X,A2),
  60.         Z1 is Z - 1, tak(Z1,X,Y,A3),
  61.         tak(A1,A2,A3,A).
  62.  
  63. -------------------------------------------------------------------------------
  64.  
  65. /* C version of fib benchmark */
  66.  
  67. #include <stdio.h>
  68.  
  69. int fib(x)
  70. int x;
  71. {
  72.   if (x <= 1) return 1;
  73.   return (fib(x-1)+fib(x-2));
  74. }
  75.  
  76. main()
  77. {
  78.   printf("%d\n", fib(30));
  79. }
  80.  
  81. -------------------------------------------------------------------------------
  82.  
  83. /* Prolog version of fib benchmark */
  84.  
  85. main :- fib(30,N), write(N), nl.
  86.  
  87. fib(N,F) :- N =< 1, F = 1.
  88. fib(N,F) :- N > 1,
  89.         N1 is N - 1, fib(N1,F1),
  90.         N2 is N - 2, fib(N2,F2),
  91.         F is F1 + F2.
  92.  
  93. -------------------------------------------------------------------------------
  94.  
  95. /* C version of hanoi benchmark */
  96.  
  97. #include <stdio.h>
  98.  
  99. han(n,a,b,c)
  100. {
  101.    int n1;
  102.  
  103.    if (n<=0) return;
  104.    n1 = n-1;
  105.    han(n1,a,c,b);
  106.    han(n1,c,b,a);
  107. }
  108.  
  109. main()
  110. {
  111.   han(20,1,2,3);
  112. }
  113.  
  114. -------------------------------------------------------------------------------
  115.  
  116. /* Prolog version of hanoi benchmark */
  117.  
  118. main :- han(20,1,2,3).
  119.  
  120. han(N,_,_,_) :- N=<0.
  121. han(N,A,B,C) :- N>0,
  122.         N1 is N - 1,
  123.         han(N1,A,C,B),
  124.         han(N1,C,B,A).
  125.  
  126. -------------------------------------------------------------------------------
  127.  
  128. /* C version of quicksort benchmark */
  129.  
  130. #include <stdio.h>
  131.  
  132. int ilist[50] = {27,74,17,33,94,18,46,83,65, 2,
  133.                  32,53,28,85,99,47,28,82, 6,11,
  134.                  55,29,39,81,90,37,10, 0,66,51,
  135.                   7,21,85,27,31,63,75, 4,95,99,
  136.                  11,28,61,74,18,92,40,53,59, 8};
  137.  
  138. int list[50];
  139.  
  140. qsort(l, r)
  141. int l, r;
  142. {
  143.    int v, t, i, j;
  144.  
  145.    if (l<r) {
  146.     v=list[l]; i=l; j=r+1;
  147.     do {
  148.         do i++; while (list[i]<v);
  149.         do j--; while (list[j]>v);
  150.         t=list[j]; list[j]=list[i]; list[i]=t;
  151.     } while (j>i);
  152.     list[i]=list[j]; list[j]=list[l]; list[l]=t;
  153.     qsort(l,j-1);
  154.     qsort(j+1,r);
  155.    }
  156. }
  157.  
  158. main()
  159. {
  160.    int i,j;
  161.  
  162.    for(j=0; j<10000; j++) {
  163.        for(i=0;i<50;i++) list[i]=ilist[i];
  164.        qsort(0,49);
  165.    }
  166.    for(i=0; i<50; i++) printf("%d ",list[i]);
  167.    printf("\n");
  168. }
  169.  
  170. -------------------------------------------------------------------------------
  171.  
  172. /* Prolog version of quicksort benchmark */
  173.  
  174. main :- range(1,I,9999), qsort(_), fail.
  175. main :- qsort(S), write(S), nl.
  176.  
  177. range(L,L,H).
  178. range(L,I,H) :- L<H, L1 is L+1, range(L1,I,H).
  179.  
  180. qsort(S) :- qsort([27,74,17,33,94,18,46,83,65, 2,
  181.            32,53,28,85,99,47,28,82, 6,11,
  182.            55,29,39,81,90,37,10, 0,66,51,
  183.             7,21,85,27,31,63,75, 4,95,99,
  184.            11,28,61,74,18,92,40,53,59, 8],S,[]).
  185.  
  186. qsort([X|L],R,R0) :-
  187.     partition(L,X,L1,L2),
  188.     qsort(L2,R1,R0),
  189.     qsort(L1,R,[X|R1]).
  190. qsort([],R,R).
  191.  
  192. partition([Y|L],X,[Y|L1],L2) :- Y=<X, partition(L,X,L1,L2).
  193. partition([Y|L],X,L1,[Y|L2]) :- Y>X,  partition(L,X,L1,L2).
  194. partition([],_,[],[]).
  195.  
  196. -------------------------------------------------------------------------------
  197.